SetPlantsManagement Subroutine

public subroutine SetPlantsManagement(file, begin, end)

Set variables and options to manage plants. Basically two options are available:

  1. Regular thinning time interval and intensity. The percentage of plants is removed every time interval.
  2. Specific dates when applying a given thinning intensity

A different option can be specified for each stand (cell).

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: file

file to configure plants management

type(DateTime), intent(in) :: begin

simulation starting date

type(DateTime), intent(in) :: end

simulation ending date


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public, ALLOCATABLE :: active_practices(:)
integer(kind=short), public :: count_practices
integer(kind=short), public :: cuts

number of cuts

integer(kind=short), public :: i
type(IniList), public :: iniDB

store configuration info

integer(kind=short), public :: interval

thinning interval (years)

integer(kind=short), public :: j
integer(kind=short), public, ALLOCATABLE :: uniques(:)

Source Code

SUBROUTINE  SetPlantsManagement &
!
(file, begin, end )

IMPLICIT NONE

!arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: file !! file to configure plants management
TYPE (DateTime), INTENT (IN) :: begin !!simulation starting date
TYPE (DateTime), INTENT(IN) :: end !!simulation ending date

!local declarations:
TYPE(IniList) :: iniDB !!store configuration info
INTEGER (KIND = short) :: i, j
INTEGER (KIND = short), ALLOCATABLE :: uniques (:)
INTEGER (KIND = short), ALLOCATABLE :: active_practices (:)
INTEGER (KIND = short) :: count_practices
INTEGER (KIND = short) :: cuts !!number of cuts 
INTEGER (KIND = short) :: interval !!thinning interval (years)
!---------------------------------------end of declarations--------------------

!load options
CALL IniOpen (file, iniDB)

!set management map
IF ( SectionIsPresent ( 'practice-map', iniDB)  ) THEN
    CALL GridByIni (iniDB, management_map, section = 'practice-map')
    
ELSE
    CALL Catch ('error', 'PlantsManagement', 'practice-map missing in configuration file')
END IF

!find unique values in management_map
CALL UniqueValues (management_map, uniques)

!search active management practices 
count_practices = 0
DO i = 1, SIZE (uniques)
    IF ( SectionIsPresent ( ToString (uniques(i)), iniDB ) ) THEN
        count_practices = count_practices + 1
    ELSE
        CALL Catch ('warning', 'PlantsManagement', 'section ' // TRIM (ToString (uniques(i)) ) // ' has no management associated' )
    END IF
END DO

ALLOCATE ( active_practices ( count_practices) )

j = 0
DO i = 1, SIZE (uniques)
    IF ( SectionIsPresent ( ToString (uniques(i)), iniDB ) ) THEN
        j = j + 1
        active_practices (j) = uniques (i)
    END IF
END DO


ALLOCATE ( practices ( (count_practices) ) )

DO i = 1, count_practices
    
    !set id
    practices (i) % id = active_practices (i)
    !check if regular interval thinning is required
    IF ( KeyIsPresent (key = 'thinning-interval', iniDB = iniDB, &
            section = ToString (active_practices(i)) ) ) THEN
             
        interval = IniReadInt  ( 'thinning-interval', iniDB, section = ToString (active_practices(i))  )
             
        !compute how many cuts to do
        cuts = (end - begin) / year / interval
             
        ALLOCATE (   practices (i) % cuts (cuts)   )
             
        DO j = 1, cuts
                 
            !set date and time of thinning
            practices (i) % cuts (j) % time = begin  + INT( j * interval * year)
                 
            !set percentage of thinning
            practices (i) % cuts (j) % intensity = IniReadReal &
                ( 'thinning-intensity', iniDB, section = ToString (active_practices(i)) )
                 
            !detect clear-cutting and reforestation
            IF ( practices (i) % cuts (j) % intensity == 100. ) THEN 
                practices (i) % cuts (j) % reforestation = .TRUE.
                !read parameters for reforestation
                practices (i) % cuts (j) % species = &
                    IniReadInt ( 'species', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % density = &
                    IniReadReal ( 'density', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % age = &
                    IniReadReal ( 'age', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % dbh = &
                    IniReadReal ( 'dbh', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % height = &
                    IniReadReal ( 'height', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % stem_biomass = &
                    IniReadReal ( 'stem-biomass', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % root_biomass = &
                    IniReadReal ( 'root-biomass', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % leaf_biomass = &
                    IniReadReal ( 'leaf-biomass', iniDB, section = ToString (active_practices(i)) )
                practices (i) % cuts (j) % lai = &
                    IniReadReal ( 'lai', iniDB, section = ToString (active_practices(i)) )
                      
            ELSE
                practices (i) % cuts (j) % reforestation = .FALSE.
            END IF
                                
                 
        END DO
        
        !set time for next cut
        practices (i) % next = practices (i) % cuts (1) % time
        practices (i) % current = 0
            

    ELSE ! thinning at given dates
            cuts = GetNofSubSections ( ini = iniDB, sectionname = ToString (active_practices(i)) )
            
            ALLOCATE (   practices (i) % cuts (cuts)   )
            
            DO j = 1, cuts
                
                !set date and time of thinning
                timeString = IniReadString &
                        ( 'date', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) ) 
                
                timeString (11:) = 'T00:00:00+00:00'
                practices (i) % cuts (j) % time = timeString
                 
                !set percentage of thinning
                    practices (i) % cuts (j) % intensity = IniReadReal &
                        ( 'thinning-intensity', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                 
                    !detect clear-cutting and reforestation
                    IF ( practices (i) % cuts (j) % intensity == 100. ) THEN 
                        practices (i) % cuts (j) % reforestation = .TRUE.
                        !read parameters for reforestation
                        practices (i) % cuts (j) % species = &
                            IniReadInt ( 'species', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % density = &
                            IniReadReal ( 'density', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % age = &
                            IniReadReal ( 'age', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % dbh = &
                            IniReadReal ( 'dbh', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % height = &
                            IniReadReal ( 'height', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % stem_biomass = &
                            IniReadReal ( 'stem-biomass', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % root_biomass = &
                            IniReadReal ( 'root-biomass', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % leaf_biomass = &
                            IniReadReal ( 'leaf-biomass', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                        practices (i) % cuts (j) % lai = &
                            IniReadReal ( 'lai', iniDB, section = ToString (active_practices(i)), subsection = 'cut' // ToString (j) )
                      
                    ELSE
                        practices (i) % cuts (j) % reforestation = .FALSE.
                    END IF
                              
            END DO    
            
            !set time for next cut
            practices (i) % next = practices (i) % cuts (1) % time
            practices (i) % current = 0
                 
    END IF
         
 
END DO


!freememory
DEALLOCATE ( uniques )
DEALLOCATE ( active_practices )

!close option file
CALL IniClose (iniDB)

RETURN
END SUBROUTINE SetPlantsManagement